{-# 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.PrivateNetworks.DeactivateDeviceIdentifier
(
DeactivateDeviceIdentifier (..),
newDeactivateDeviceIdentifier,
deactivateDeviceIdentifier_clientToken,
deactivateDeviceIdentifier_deviceIdentifierArn,
DeactivateDeviceIdentifierResponse (..),
newDeactivateDeviceIdentifierResponse,
deactivateDeviceIdentifierResponse_httpStatus,
deactivateDeviceIdentifierResponse_deviceIdentifier,
)
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 Amazonka.PrivateNetworks.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data DeactivateDeviceIdentifier = DeactivateDeviceIdentifier'
{
DeactivateDeviceIdentifier -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
DeactivateDeviceIdentifier -> Text
deviceIdentifierArn :: Prelude.Text
}
deriving (DeactivateDeviceIdentifier -> DeactivateDeviceIdentifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeactivateDeviceIdentifier -> DeactivateDeviceIdentifier -> Bool
$c/= :: DeactivateDeviceIdentifier -> DeactivateDeviceIdentifier -> Bool
== :: DeactivateDeviceIdentifier -> DeactivateDeviceIdentifier -> Bool
$c== :: DeactivateDeviceIdentifier -> DeactivateDeviceIdentifier -> Bool
Prelude.Eq, ReadPrec [DeactivateDeviceIdentifier]
ReadPrec DeactivateDeviceIdentifier
Int -> ReadS DeactivateDeviceIdentifier
ReadS [DeactivateDeviceIdentifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeactivateDeviceIdentifier]
$creadListPrec :: ReadPrec [DeactivateDeviceIdentifier]
readPrec :: ReadPrec DeactivateDeviceIdentifier
$creadPrec :: ReadPrec DeactivateDeviceIdentifier
readList :: ReadS [DeactivateDeviceIdentifier]
$creadList :: ReadS [DeactivateDeviceIdentifier]
readsPrec :: Int -> ReadS DeactivateDeviceIdentifier
$creadsPrec :: Int -> ReadS DeactivateDeviceIdentifier
Prelude.Read, Int -> DeactivateDeviceIdentifier -> ShowS
[DeactivateDeviceIdentifier] -> ShowS
DeactivateDeviceIdentifier -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeactivateDeviceIdentifier] -> ShowS
$cshowList :: [DeactivateDeviceIdentifier] -> ShowS
show :: DeactivateDeviceIdentifier -> String
$cshow :: DeactivateDeviceIdentifier -> String
showsPrec :: Int -> DeactivateDeviceIdentifier -> ShowS
$cshowsPrec :: Int -> DeactivateDeviceIdentifier -> ShowS
Prelude.Show, forall x.
Rep DeactivateDeviceIdentifier x -> DeactivateDeviceIdentifier
forall x.
DeactivateDeviceIdentifier -> Rep DeactivateDeviceIdentifier x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeactivateDeviceIdentifier x -> DeactivateDeviceIdentifier
$cfrom :: forall x.
DeactivateDeviceIdentifier -> Rep DeactivateDeviceIdentifier x
Prelude.Generic)
newDeactivateDeviceIdentifier ::
Prelude.Text ->
DeactivateDeviceIdentifier
newDeactivateDeviceIdentifier :: Text -> DeactivateDeviceIdentifier
newDeactivateDeviceIdentifier Text
pDeviceIdentifierArn_ =
DeactivateDeviceIdentifier'
{ $sel:clientToken:DeactivateDeviceIdentifier' :: Maybe Text
clientToken =
forall a. Maybe a
Prelude.Nothing,
$sel:deviceIdentifierArn:DeactivateDeviceIdentifier' :: Text
deviceIdentifierArn = Text
pDeviceIdentifierArn_
}
deactivateDeviceIdentifier_clientToken :: Lens.Lens' DeactivateDeviceIdentifier (Prelude.Maybe Prelude.Text)
deactivateDeviceIdentifier_clientToken :: Lens' DeactivateDeviceIdentifier (Maybe Text)
deactivateDeviceIdentifier_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeactivateDeviceIdentifier' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:DeactivateDeviceIdentifier' :: DeactivateDeviceIdentifier -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: DeactivateDeviceIdentifier
s@DeactivateDeviceIdentifier' {} Maybe Text
a -> DeactivateDeviceIdentifier
s {$sel:clientToken:DeactivateDeviceIdentifier' :: Maybe Text
clientToken = Maybe Text
a} :: DeactivateDeviceIdentifier)
deactivateDeviceIdentifier_deviceIdentifierArn :: Lens.Lens' DeactivateDeviceIdentifier Prelude.Text
deactivateDeviceIdentifier_deviceIdentifierArn :: Lens' DeactivateDeviceIdentifier Text
deactivateDeviceIdentifier_deviceIdentifierArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeactivateDeviceIdentifier' {Text
deviceIdentifierArn :: Text
$sel:deviceIdentifierArn:DeactivateDeviceIdentifier' :: DeactivateDeviceIdentifier -> Text
deviceIdentifierArn} -> Text
deviceIdentifierArn) (\s :: DeactivateDeviceIdentifier
s@DeactivateDeviceIdentifier' {} Text
a -> DeactivateDeviceIdentifier
s {$sel:deviceIdentifierArn:DeactivateDeviceIdentifier' :: Text
deviceIdentifierArn = Text
a} :: DeactivateDeviceIdentifier)
instance Core.AWSRequest DeactivateDeviceIdentifier where
type
AWSResponse DeactivateDeviceIdentifier =
DeactivateDeviceIdentifierResponse
request :: (Service -> Service)
-> DeactivateDeviceIdentifier -> Request DeactivateDeviceIdentifier
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 DeactivateDeviceIdentifier
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse DeactivateDeviceIdentifier)))
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 ->
Int -> DeviceIdentifier -> DeactivateDeviceIdentifierResponse
DeactivateDeviceIdentifierResponse'
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))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"deviceIdentifier")
)
instance Prelude.Hashable DeactivateDeviceIdentifier where
hashWithSalt :: Int -> DeactivateDeviceIdentifier -> Int
hashWithSalt Int
_salt DeactivateDeviceIdentifier' {Maybe Text
Text
deviceIdentifierArn :: Text
clientToken :: Maybe Text
$sel:deviceIdentifierArn:DeactivateDeviceIdentifier' :: DeactivateDeviceIdentifier -> Text
$sel:clientToken:DeactivateDeviceIdentifier' :: DeactivateDeviceIdentifier -> Maybe Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
deviceIdentifierArn
instance Prelude.NFData DeactivateDeviceIdentifier where
rnf :: DeactivateDeviceIdentifier -> ()
rnf DeactivateDeviceIdentifier' {Maybe Text
Text
deviceIdentifierArn :: Text
clientToken :: Maybe Text
$sel:deviceIdentifierArn:DeactivateDeviceIdentifier' :: DeactivateDeviceIdentifier -> Text
$sel:clientToken:DeactivateDeviceIdentifier' :: DeactivateDeviceIdentifier -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
deviceIdentifierArn
instance Data.ToHeaders DeactivateDeviceIdentifier where
toHeaders :: DeactivateDeviceIdentifier -> 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.ToJSON DeactivateDeviceIdentifier where
toJSON :: DeactivateDeviceIdentifier -> Value
toJSON DeactivateDeviceIdentifier' {Maybe Text
Text
deviceIdentifierArn :: Text
clientToken :: Maybe Text
$sel:deviceIdentifierArn:DeactivateDeviceIdentifier' :: DeactivateDeviceIdentifier -> Text
$sel:clientToken:DeactivateDeviceIdentifier' :: DeactivateDeviceIdentifier -> Maybe Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"clientToken" 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
clientToken,
forall a. a -> Maybe a
Prelude.Just
(Key
"deviceIdentifierArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
deviceIdentifierArn)
]
)
instance Data.ToPath DeactivateDeviceIdentifier where
toPath :: DeactivateDeviceIdentifier -> ByteString
toPath =
forall a b. a -> b -> a
Prelude.const ByteString
"/v1/device-identifiers/deactivate"
instance Data.ToQuery DeactivateDeviceIdentifier where
toQuery :: DeactivateDeviceIdentifier -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data DeactivateDeviceIdentifierResponse = DeactivateDeviceIdentifierResponse'
{
DeactivateDeviceIdentifierResponse -> Int
httpStatus :: Prelude.Int,
DeactivateDeviceIdentifierResponse -> DeviceIdentifier
deviceIdentifier :: DeviceIdentifier
}
deriving (DeactivateDeviceIdentifierResponse
-> DeactivateDeviceIdentifierResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeactivateDeviceIdentifierResponse
-> DeactivateDeviceIdentifierResponse -> Bool
$c/= :: DeactivateDeviceIdentifierResponse
-> DeactivateDeviceIdentifierResponse -> Bool
== :: DeactivateDeviceIdentifierResponse
-> DeactivateDeviceIdentifierResponse -> Bool
$c== :: DeactivateDeviceIdentifierResponse
-> DeactivateDeviceIdentifierResponse -> Bool
Prelude.Eq, Int -> DeactivateDeviceIdentifierResponse -> ShowS
[DeactivateDeviceIdentifierResponse] -> ShowS
DeactivateDeviceIdentifierResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeactivateDeviceIdentifierResponse] -> ShowS
$cshowList :: [DeactivateDeviceIdentifierResponse] -> ShowS
show :: DeactivateDeviceIdentifierResponse -> String
$cshow :: DeactivateDeviceIdentifierResponse -> String
showsPrec :: Int -> DeactivateDeviceIdentifierResponse -> ShowS
$cshowsPrec :: Int -> DeactivateDeviceIdentifierResponse -> ShowS
Prelude.Show, forall x.
Rep DeactivateDeviceIdentifierResponse x
-> DeactivateDeviceIdentifierResponse
forall x.
DeactivateDeviceIdentifierResponse
-> Rep DeactivateDeviceIdentifierResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeactivateDeviceIdentifierResponse x
-> DeactivateDeviceIdentifierResponse
$cfrom :: forall x.
DeactivateDeviceIdentifierResponse
-> Rep DeactivateDeviceIdentifierResponse x
Prelude.Generic)
newDeactivateDeviceIdentifierResponse ::
Prelude.Int ->
DeviceIdentifier ->
DeactivateDeviceIdentifierResponse
newDeactivateDeviceIdentifierResponse :: Int -> DeviceIdentifier -> DeactivateDeviceIdentifierResponse
newDeactivateDeviceIdentifierResponse
Int
pHttpStatus_
DeviceIdentifier
pDeviceIdentifier_ =
DeactivateDeviceIdentifierResponse'
{ $sel:httpStatus:DeactivateDeviceIdentifierResponse' :: Int
httpStatus =
Int
pHttpStatus_,
$sel:deviceIdentifier:DeactivateDeviceIdentifierResponse' :: DeviceIdentifier
deviceIdentifier = DeviceIdentifier
pDeviceIdentifier_
}
deactivateDeviceIdentifierResponse_httpStatus :: Lens.Lens' DeactivateDeviceIdentifierResponse Prelude.Int
deactivateDeviceIdentifierResponse_httpStatus :: Lens' DeactivateDeviceIdentifierResponse Int
deactivateDeviceIdentifierResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeactivateDeviceIdentifierResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeactivateDeviceIdentifierResponse' :: DeactivateDeviceIdentifierResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeactivateDeviceIdentifierResponse
s@DeactivateDeviceIdentifierResponse' {} Int
a -> DeactivateDeviceIdentifierResponse
s {$sel:httpStatus:DeactivateDeviceIdentifierResponse' :: Int
httpStatus = Int
a} :: DeactivateDeviceIdentifierResponse)
deactivateDeviceIdentifierResponse_deviceIdentifier :: Lens.Lens' DeactivateDeviceIdentifierResponse DeviceIdentifier
deactivateDeviceIdentifierResponse_deviceIdentifier :: Lens' DeactivateDeviceIdentifierResponse DeviceIdentifier
deactivateDeviceIdentifierResponse_deviceIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeactivateDeviceIdentifierResponse' {DeviceIdentifier
deviceIdentifier :: DeviceIdentifier
$sel:deviceIdentifier:DeactivateDeviceIdentifierResponse' :: DeactivateDeviceIdentifierResponse -> DeviceIdentifier
deviceIdentifier} -> DeviceIdentifier
deviceIdentifier) (\s :: DeactivateDeviceIdentifierResponse
s@DeactivateDeviceIdentifierResponse' {} DeviceIdentifier
a -> DeactivateDeviceIdentifierResponse
s {$sel:deviceIdentifier:DeactivateDeviceIdentifierResponse' :: DeviceIdentifier
deviceIdentifier = DeviceIdentifier
a} :: DeactivateDeviceIdentifierResponse)
instance
Prelude.NFData
DeactivateDeviceIdentifierResponse
where
rnf :: DeactivateDeviceIdentifierResponse -> ()
rnf DeactivateDeviceIdentifierResponse' {Int
DeviceIdentifier
deviceIdentifier :: DeviceIdentifier
httpStatus :: Int
$sel:deviceIdentifier:DeactivateDeviceIdentifierResponse' :: DeactivateDeviceIdentifierResponse -> DeviceIdentifier
$sel:httpStatus:DeactivateDeviceIdentifierResponse' :: DeactivateDeviceIdentifierResponse -> Int
..} =
forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf DeviceIdentifier
deviceIdentifier