{-# 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.WorkSpacesWeb.DisassociateNetworkSettings
(
DisassociateNetworkSettings (..),
newDisassociateNetworkSettings,
disassociateNetworkSettings_portalArn,
DisassociateNetworkSettingsResponse (..),
newDisassociateNetworkSettingsResponse,
disassociateNetworkSettingsResponse_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 qualified Amazonka.Response as Response
import Amazonka.WorkSpacesWeb.Types
data DisassociateNetworkSettings = DisassociateNetworkSettings'
{
DisassociateNetworkSettings -> Text
portalArn :: Prelude.Text
}
deriving (DisassociateNetworkSettings -> DisassociateNetworkSettings -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateNetworkSettings -> DisassociateNetworkSettings -> Bool
$c/= :: DisassociateNetworkSettings -> DisassociateNetworkSettings -> Bool
== :: DisassociateNetworkSettings -> DisassociateNetworkSettings -> Bool
$c== :: DisassociateNetworkSettings -> DisassociateNetworkSettings -> Bool
Prelude.Eq, ReadPrec [DisassociateNetworkSettings]
ReadPrec DisassociateNetworkSettings
Int -> ReadS DisassociateNetworkSettings
ReadS [DisassociateNetworkSettings]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateNetworkSettings]
$creadListPrec :: ReadPrec [DisassociateNetworkSettings]
readPrec :: ReadPrec DisassociateNetworkSettings
$creadPrec :: ReadPrec DisassociateNetworkSettings
readList :: ReadS [DisassociateNetworkSettings]
$creadList :: ReadS [DisassociateNetworkSettings]
readsPrec :: Int -> ReadS DisassociateNetworkSettings
$creadsPrec :: Int -> ReadS DisassociateNetworkSettings
Prelude.Read, Int -> DisassociateNetworkSettings -> ShowS
[DisassociateNetworkSettings] -> ShowS
DisassociateNetworkSettings -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateNetworkSettings] -> ShowS
$cshowList :: [DisassociateNetworkSettings] -> ShowS
show :: DisassociateNetworkSettings -> String
$cshow :: DisassociateNetworkSettings -> String
showsPrec :: Int -> DisassociateNetworkSettings -> ShowS
$cshowsPrec :: Int -> DisassociateNetworkSettings -> ShowS
Prelude.Show, forall x.
Rep DisassociateNetworkSettings x -> DisassociateNetworkSettings
forall x.
DisassociateNetworkSettings -> Rep DisassociateNetworkSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisassociateNetworkSettings x -> DisassociateNetworkSettings
$cfrom :: forall x.
DisassociateNetworkSettings -> Rep DisassociateNetworkSettings x
Prelude.Generic)
newDisassociateNetworkSettings ::
Prelude.Text ->
DisassociateNetworkSettings
newDisassociateNetworkSettings :: Text -> DisassociateNetworkSettings
newDisassociateNetworkSettings Text
pPortalArn_ =
DisassociateNetworkSettings'
{ $sel:portalArn:DisassociateNetworkSettings' :: Text
portalArn =
Text
pPortalArn_
}
disassociateNetworkSettings_portalArn :: Lens.Lens' DisassociateNetworkSettings Prelude.Text
disassociateNetworkSettings_portalArn :: Lens' DisassociateNetworkSettings Text
disassociateNetworkSettings_portalArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateNetworkSettings' {Text
portalArn :: Text
$sel:portalArn:DisassociateNetworkSettings' :: DisassociateNetworkSettings -> Text
portalArn} -> Text
portalArn) (\s :: DisassociateNetworkSettings
s@DisassociateNetworkSettings' {} Text
a -> DisassociateNetworkSettings
s {$sel:portalArn:DisassociateNetworkSettings' :: Text
portalArn = Text
a} :: DisassociateNetworkSettings)
instance Core.AWSRequest DisassociateNetworkSettings where
type
AWSResponse DisassociateNetworkSettings =
DisassociateNetworkSettingsResponse
request :: (Service -> Service)
-> DisassociateNetworkSettings
-> Request DisassociateNetworkSettings
request Service -> Service
overrides =
forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DisassociateNetworkSettings
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse DisassociateNetworkSettings)))
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 -> DisassociateNetworkSettingsResponse
DisassociateNetworkSettingsResponse'
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 DisassociateNetworkSettings where
hashWithSalt :: Int -> DisassociateNetworkSettings -> Int
hashWithSalt Int
_salt DisassociateNetworkSettings' {Text
portalArn :: Text
$sel:portalArn:DisassociateNetworkSettings' :: DisassociateNetworkSettings -> Text
..} =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
portalArn
instance Prelude.NFData DisassociateNetworkSettings where
rnf :: DisassociateNetworkSettings -> ()
rnf DisassociateNetworkSettings' {Text
portalArn :: Text
$sel:portalArn:DisassociateNetworkSettings' :: DisassociateNetworkSettings -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
portalArn
instance Data.ToHeaders DisassociateNetworkSettings where
toHeaders :: DisassociateNetworkSettings -> ResponseHeaders
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToPath DisassociateNetworkSettings where
toPath :: DisassociateNetworkSettings -> ByteString
toPath DisassociateNetworkSettings' {Text
portalArn :: Text
$sel:portalArn:DisassociateNetworkSettings' :: DisassociateNetworkSettings -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"/portals/",
forall a. ToByteString a => a -> ByteString
Data.toBS Text
portalArn,
ByteString
"/networkSettings"
]
instance Data.ToQuery DisassociateNetworkSettings where
toQuery :: DisassociateNetworkSettings -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data DisassociateNetworkSettingsResponse = DisassociateNetworkSettingsResponse'
{
DisassociateNetworkSettingsResponse -> Int
httpStatus :: Prelude.Int
}
deriving (DisassociateNetworkSettingsResponse
-> DisassociateNetworkSettingsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateNetworkSettingsResponse
-> DisassociateNetworkSettingsResponse -> Bool
$c/= :: DisassociateNetworkSettingsResponse
-> DisassociateNetworkSettingsResponse -> Bool
== :: DisassociateNetworkSettingsResponse
-> DisassociateNetworkSettingsResponse -> Bool
$c== :: DisassociateNetworkSettingsResponse
-> DisassociateNetworkSettingsResponse -> Bool
Prelude.Eq, ReadPrec [DisassociateNetworkSettingsResponse]
ReadPrec DisassociateNetworkSettingsResponse
Int -> ReadS DisassociateNetworkSettingsResponse
ReadS [DisassociateNetworkSettingsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateNetworkSettingsResponse]
$creadListPrec :: ReadPrec [DisassociateNetworkSettingsResponse]
readPrec :: ReadPrec DisassociateNetworkSettingsResponse
$creadPrec :: ReadPrec DisassociateNetworkSettingsResponse
readList :: ReadS [DisassociateNetworkSettingsResponse]
$creadList :: ReadS [DisassociateNetworkSettingsResponse]
readsPrec :: Int -> ReadS DisassociateNetworkSettingsResponse
$creadsPrec :: Int -> ReadS DisassociateNetworkSettingsResponse
Prelude.Read, Int -> DisassociateNetworkSettingsResponse -> ShowS
[DisassociateNetworkSettingsResponse] -> ShowS
DisassociateNetworkSettingsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateNetworkSettingsResponse] -> ShowS
$cshowList :: [DisassociateNetworkSettingsResponse] -> ShowS
show :: DisassociateNetworkSettingsResponse -> String
$cshow :: DisassociateNetworkSettingsResponse -> String
showsPrec :: Int -> DisassociateNetworkSettingsResponse -> ShowS
$cshowsPrec :: Int -> DisassociateNetworkSettingsResponse -> ShowS
Prelude.Show, forall x.
Rep DisassociateNetworkSettingsResponse x
-> DisassociateNetworkSettingsResponse
forall x.
DisassociateNetworkSettingsResponse
-> Rep DisassociateNetworkSettingsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisassociateNetworkSettingsResponse x
-> DisassociateNetworkSettingsResponse
$cfrom :: forall x.
DisassociateNetworkSettingsResponse
-> Rep DisassociateNetworkSettingsResponse x
Prelude.Generic)
newDisassociateNetworkSettingsResponse ::
Prelude.Int ->
DisassociateNetworkSettingsResponse
newDisassociateNetworkSettingsResponse :: Int -> DisassociateNetworkSettingsResponse
newDisassociateNetworkSettingsResponse Int
pHttpStatus_ =
DisassociateNetworkSettingsResponse'
{ $sel:httpStatus:DisassociateNetworkSettingsResponse' :: Int
httpStatus =
Int
pHttpStatus_
}
disassociateNetworkSettingsResponse_httpStatus :: Lens.Lens' DisassociateNetworkSettingsResponse Prelude.Int
disassociateNetworkSettingsResponse_httpStatus :: Lens' DisassociateNetworkSettingsResponse Int
disassociateNetworkSettingsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateNetworkSettingsResponse' {Int
httpStatus :: Int
$sel:httpStatus:DisassociateNetworkSettingsResponse' :: DisassociateNetworkSettingsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DisassociateNetworkSettingsResponse
s@DisassociateNetworkSettingsResponse' {} Int
a -> DisassociateNetworkSettingsResponse
s {$sel:httpStatus:DisassociateNetworkSettingsResponse' :: Int
httpStatus = Int
a} :: DisassociateNetworkSettingsResponse)
instance
Prelude.NFData
DisassociateNetworkSettingsResponse
where
rnf :: DisassociateNetworkSettingsResponse -> ()
rnf DisassociateNetworkSettingsResponse' {Int
httpStatus :: Int
$sel:httpStatus:DisassociateNetworkSettingsResponse' :: DisassociateNetworkSettingsResponse -> Int
..} =
forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus