{-# 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.MediaLive.UpdateInputDevice
(
UpdateInputDevice' (..),
newUpdateInputDevice',
updateInputDevice'_hdDeviceSettings,
updateInputDevice'_name,
updateInputDevice'_uhdDeviceSettings,
updateInputDevice'_inputDeviceId,
UpdateInputDeviceResponse (..),
newUpdateInputDeviceResponse,
updateInputDeviceResponse_arn,
updateInputDeviceResponse_connectionState,
updateInputDeviceResponse_deviceSettingsSyncState,
updateInputDeviceResponse_deviceUpdateStatus,
updateInputDeviceResponse_hdDeviceSettings,
updateInputDeviceResponse_id,
updateInputDeviceResponse_macAddress,
updateInputDeviceResponse_name,
updateInputDeviceResponse_networkSettings,
updateInputDeviceResponse_serialNumber,
updateInputDeviceResponse_type,
updateInputDeviceResponse_uhdDeviceSettings,
updateInputDeviceResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MediaLive.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data UpdateInputDevice' = UpdateInputDevice''
{
UpdateInputDevice' -> Maybe InputDeviceConfigurableSettings
hdDeviceSettings :: Prelude.Maybe InputDeviceConfigurableSettings,
UpdateInputDevice' -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
UpdateInputDevice' -> Maybe InputDeviceConfigurableSettings
uhdDeviceSettings :: Prelude.Maybe InputDeviceConfigurableSettings,
UpdateInputDevice' -> Text
inputDeviceId :: Prelude.Text
}
deriving (UpdateInputDevice' -> UpdateInputDevice' -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateInputDevice' -> UpdateInputDevice' -> Bool
$c/= :: UpdateInputDevice' -> UpdateInputDevice' -> Bool
== :: UpdateInputDevice' -> UpdateInputDevice' -> Bool
$c== :: UpdateInputDevice' -> UpdateInputDevice' -> Bool
Prelude.Eq, ReadPrec [UpdateInputDevice']
ReadPrec UpdateInputDevice'
Int -> ReadS UpdateInputDevice'
ReadS [UpdateInputDevice']
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateInputDevice']
$creadListPrec :: ReadPrec [UpdateInputDevice']
readPrec :: ReadPrec UpdateInputDevice'
$creadPrec :: ReadPrec UpdateInputDevice'
readList :: ReadS [UpdateInputDevice']
$creadList :: ReadS [UpdateInputDevice']
readsPrec :: Int -> ReadS UpdateInputDevice'
$creadsPrec :: Int -> ReadS UpdateInputDevice'
Prelude.Read, Int -> UpdateInputDevice' -> ShowS
[UpdateInputDevice'] -> ShowS
UpdateInputDevice' -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateInputDevice'] -> ShowS
$cshowList :: [UpdateInputDevice'] -> ShowS
show :: UpdateInputDevice' -> String
$cshow :: UpdateInputDevice' -> String
showsPrec :: Int -> UpdateInputDevice' -> ShowS
$cshowsPrec :: Int -> UpdateInputDevice' -> ShowS
Prelude.Show, forall x. Rep UpdateInputDevice' x -> UpdateInputDevice'
forall x. UpdateInputDevice' -> Rep UpdateInputDevice' x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateInputDevice' x -> UpdateInputDevice'
$cfrom :: forall x. UpdateInputDevice' -> Rep UpdateInputDevice' x
Prelude.Generic)
newUpdateInputDevice' ::
Prelude.Text ->
UpdateInputDevice'
newUpdateInputDevice' :: Text -> UpdateInputDevice'
newUpdateInputDevice' Text
pInputDeviceId_ =
UpdateInputDevice''
{ $sel:hdDeviceSettings:UpdateInputDevice'' :: Maybe InputDeviceConfigurableSettings
hdDeviceSettings =
forall a. Maybe a
Prelude.Nothing,
$sel:name:UpdateInputDevice'' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
$sel:uhdDeviceSettings:UpdateInputDevice'' :: Maybe InputDeviceConfigurableSettings
uhdDeviceSettings = forall a. Maybe a
Prelude.Nothing,
$sel:inputDeviceId:UpdateInputDevice'' :: Text
inputDeviceId = Text
pInputDeviceId_
}
updateInputDevice'_hdDeviceSettings :: Lens.Lens' UpdateInputDevice' (Prelude.Maybe InputDeviceConfigurableSettings)
updateInputDevice'_hdDeviceSettings :: Lens' UpdateInputDevice' (Maybe InputDeviceConfigurableSettings)
updateInputDevice'_hdDeviceSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInputDevice'' {Maybe InputDeviceConfigurableSettings
hdDeviceSettings :: Maybe InputDeviceConfigurableSettings
$sel:hdDeviceSettings:UpdateInputDevice'' :: UpdateInputDevice' -> Maybe InputDeviceConfigurableSettings
hdDeviceSettings} -> Maybe InputDeviceConfigurableSettings
hdDeviceSettings) (\s :: UpdateInputDevice'
s@UpdateInputDevice'' {} Maybe InputDeviceConfigurableSettings
a -> UpdateInputDevice'
s {$sel:hdDeviceSettings:UpdateInputDevice'' :: Maybe InputDeviceConfigurableSettings
hdDeviceSettings = Maybe InputDeviceConfigurableSettings
a} :: UpdateInputDevice')
updateInputDevice'_name :: Lens.Lens' UpdateInputDevice' (Prelude.Maybe Prelude.Text)
updateInputDevice'_name :: Lens' UpdateInputDevice' (Maybe Text)
updateInputDevice'_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInputDevice'' {Maybe Text
name :: Maybe Text
$sel:name:UpdateInputDevice'' :: UpdateInputDevice' -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateInputDevice'
s@UpdateInputDevice'' {} Maybe Text
a -> UpdateInputDevice'
s {$sel:name:UpdateInputDevice'' :: Maybe Text
name = Maybe Text
a} :: UpdateInputDevice')
updateInputDevice'_uhdDeviceSettings :: Lens.Lens' UpdateInputDevice' (Prelude.Maybe InputDeviceConfigurableSettings)
updateInputDevice'_uhdDeviceSettings :: Lens' UpdateInputDevice' (Maybe InputDeviceConfigurableSettings)
updateInputDevice'_uhdDeviceSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInputDevice'' {Maybe InputDeviceConfigurableSettings
uhdDeviceSettings :: Maybe InputDeviceConfigurableSettings
$sel:uhdDeviceSettings:UpdateInputDevice'' :: UpdateInputDevice' -> Maybe InputDeviceConfigurableSettings
uhdDeviceSettings} -> Maybe InputDeviceConfigurableSettings
uhdDeviceSettings) (\s :: UpdateInputDevice'
s@UpdateInputDevice'' {} Maybe InputDeviceConfigurableSettings
a -> UpdateInputDevice'
s {$sel:uhdDeviceSettings:UpdateInputDevice'' :: Maybe InputDeviceConfigurableSettings
uhdDeviceSettings = Maybe InputDeviceConfigurableSettings
a} :: UpdateInputDevice')
updateInputDevice'_inputDeviceId :: Lens.Lens' UpdateInputDevice' Prelude.Text
updateInputDevice'_inputDeviceId :: Lens' UpdateInputDevice' Text
updateInputDevice'_inputDeviceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInputDevice'' {Text
inputDeviceId :: Text
$sel:inputDeviceId:UpdateInputDevice'' :: UpdateInputDevice' -> Text
inputDeviceId} -> Text
inputDeviceId) (\s :: UpdateInputDevice'
s@UpdateInputDevice'' {} Text
a -> UpdateInputDevice'
s {$sel:inputDeviceId:UpdateInputDevice'' :: Text
inputDeviceId = Text
a} :: UpdateInputDevice')
instance Core.AWSRequest UpdateInputDevice' where
type
AWSResponse UpdateInputDevice' =
UpdateInputDeviceResponse
request :: (Service -> Service)
-> UpdateInputDevice' -> Request UpdateInputDevice'
request Service -> Service
overrides =
forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateInputDevice'
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse UpdateInputDevice')))
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 Text
-> Maybe InputDeviceConnectionState
-> Maybe DeviceSettingsSyncState
-> Maybe DeviceUpdateStatus
-> Maybe InputDeviceHdSettings
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe InputDeviceNetworkSettings
-> Maybe Text
-> Maybe InputDeviceType
-> Maybe InputDeviceUhdSettings
-> Int
-> UpdateInputDeviceResponse
UpdateInputDeviceResponse'
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
"arn")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"connectionState")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"deviceSettingsSyncState")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"deviceUpdateStatus")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"hdDeviceSettings")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"id")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"macAddress")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"name")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"networkSettings")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"serialNumber")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"type")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"uhdDeviceSettings")
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 UpdateInputDevice' where
hashWithSalt :: Int -> UpdateInputDevice' -> Int
hashWithSalt Int
_salt UpdateInputDevice'' {Maybe Text
Maybe InputDeviceConfigurableSettings
Text
inputDeviceId :: Text
uhdDeviceSettings :: Maybe InputDeviceConfigurableSettings
name :: Maybe Text
hdDeviceSettings :: Maybe InputDeviceConfigurableSettings
$sel:inputDeviceId:UpdateInputDevice'' :: UpdateInputDevice' -> Text
$sel:uhdDeviceSettings:UpdateInputDevice'' :: UpdateInputDevice' -> Maybe InputDeviceConfigurableSettings
$sel:name:UpdateInputDevice'' :: UpdateInputDevice' -> Maybe Text
$sel:hdDeviceSettings:UpdateInputDevice'' :: UpdateInputDevice' -> Maybe InputDeviceConfigurableSettings
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InputDeviceConfigurableSettings
hdDeviceSettings
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InputDeviceConfigurableSettings
uhdDeviceSettings
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
inputDeviceId
instance Prelude.NFData UpdateInputDevice' where
rnf :: UpdateInputDevice' -> ()
rnf UpdateInputDevice'' {Maybe Text
Maybe InputDeviceConfigurableSettings
Text
inputDeviceId :: Text
uhdDeviceSettings :: Maybe InputDeviceConfigurableSettings
name :: Maybe Text
hdDeviceSettings :: Maybe InputDeviceConfigurableSettings
$sel:inputDeviceId:UpdateInputDevice'' :: UpdateInputDevice' -> Text
$sel:uhdDeviceSettings:UpdateInputDevice'' :: UpdateInputDevice' -> Maybe InputDeviceConfigurableSettings
$sel:name:UpdateInputDevice'' :: UpdateInputDevice' -> Maybe Text
$sel:hdDeviceSettings:UpdateInputDevice'' :: UpdateInputDevice' -> Maybe InputDeviceConfigurableSettings
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe InputDeviceConfigurableSettings
hdDeviceSettings
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InputDeviceConfigurableSettings
uhdDeviceSettings
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
inputDeviceId
instance Data.ToHeaders UpdateInputDevice' where
toHeaders :: UpdateInputDevice' -> 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 UpdateInputDevice' where
toJSON :: UpdateInputDevice' -> Value
toJSON UpdateInputDevice'' {Maybe Text
Maybe InputDeviceConfigurableSettings
Text
inputDeviceId :: Text
uhdDeviceSettings :: Maybe InputDeviceConfigurableSettings
name :: Maybe Text
hdDeviceSettings :: Maybe InputDeviceConfigurableSettings
$sel:inputDeviceId:UpdateInputDevice'' :: UpdateInputDevice' -> Text
$sel:uhdDeviceSettings:UpdateInputDevice'' :: UpdateInputDevice' -> Maybe InputDeviceConfigurableSettings
$sel:name:UpdateInputDevice'' :: UpdateInputDevice' -> Maybe Text
$sel:hdDeviceSettings:UpdateInputDevice'' :: UpdateInputDevice' -> Maybe InputDeviceConfigurableSettings
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"hdDeviceSettings" 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 InputDeviceConfigurableSettings
hdDeviceSettings,
(Key
"name" 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
name,
(Key
"uhdDeviceSettings" 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 InputDeviceConfigurableSettings
uhdDeviceSettings
]
)
instance Data.ToPath UpdateInputDevice' where
toPath :: UpdateInputDevice' -> ByteString
toPath UpdateInputDevice'' {Maybe Text
Maybe InputDeviceConfigurableSettings
Text
inputDeviceId :: Text
uhdDeviceSettings :: Maybe InputDeviceConfigurableSettings
name :: Maybe Text
hdDeviceSettings :: Maybe InputDeviceConfigurableSettings
$sel:inputDeviceId:UpdateInputDevice'' :: UpdateInputDevice' -> Text
$sel:uhdDeviceSettings:UpdateInputDevice'' :: UpdateInputDevice' -> Maybe InputDeviceConfigurableSettings
$sel:name:UpdateInputDevice'' :: UpdateInputDevice' -> Maybe Text
$sel:hdDeviceSettings:UpdateInputDevice'' :: UpdateInputDevice' -> Maybe InputDeviceConfigurableSettings
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ByteString
"/prod/inputDevices/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
inputDeviceId]
instance Data.ToQuery UpdateInputDevice' where
toQuery :: UpdateInputDevice' -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data UpdateInputDeviceResponse = UpdateInputDeviceResponse'
{
UpdateInputDeviceResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
UpdateInputDeviceResponse -> Maybe InputDeviceConnectionState
connectionState :: Prelude.Maybe InputDeviceConnectionState,
UpdateInputDeviceResponse -> Maybe DeviceSettingsSyncState
deviceSettingsSyncState :: Prelude.Maybe DeviceSettingsSyncState,
UpdateInputDeviceResponse -> Maybe DeviceUpdateStatus
deviceUpdateStatus :: Prelude.Maybe DeviceUpdateStatus,
UpdateInputDeviceResponse -> Maybe InputDeviceHdSettings
hdDeviceSettings :: Prelude.Maybe InputDeviceHdSettings,
UpdateInputDeviceResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
UpdateInputDeviceResponse -> Maybe Text
macAddress :: Prelude.Maybe Prelude.Text,
UpdateInputDeviceResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
UpdateInputDeviceResponse -> Maybe InputDeviceNetworkSettings
networkSettings :: Prelude.Maybe InputDeviceNetworkSettings,
UpdateInputDeviceResponse -> Maybe Text
serialNumber :: Prelude.Maybe Prelude.Text,
UpdateInputDeviceResponse -> Maybe InputDeviceType
type' :: Prelude.Maybe InputDeviceType,
UpdateInputDeviceResponse -> Maybe InputDeviceUhdSettings
uhdDeviceSettings :: Prelude.Maybe InputDeviceUhdSettings,
UpdateInputDeviceResponse -> Int
httpStatus :: Prelude.Int
}
deriving (UpdateInputDeviceResponse -> UpdateInputDeviceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateInputDeviceResponse -> UpdateInputDeviceResponse -> Bool
$c/= :: UpdateInputDeviceResponse -> UpdateInputDeviceResponse -> Bool
== :: UpdateInputDeviceResponse -> UpdateInputDeviceResponse -> Bool
$c== :: UpdateInputDeviceResponse -> UpdateInputDeviceResponse -> Bool
Prelude.Eq, ReadPrec [UpdateInputDeviceResponse]
ReadPrec UpdateInputDeviceResponse
Int -> ReadS UpdateInputDeviceResponse
ReadS [UpdateInputDeviceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateInputDeviceResponse]
$creadListPrec :: ReadPrec [UpdateInputDeviceResponse]
readPrec :: ReadPrec UpdateInputDeviceResponse
$creadPrec :: ReadPrec UpdateInputDeviceResponse
readList :: ReadS [UpdateInputDeviceResponse]
$creadList :: ReadS [UpdateInputDeviceResponse]
readsPrec :: Int -> ReadS UpdateInputDeviceResponse
$creadsPrec :: Int -> ReadS UpdateInputDeviceResponse
Prelude.Read, Int -> UpdateInputDeviceResponse -> ShowS
[UpdateInputDeviceResponse] -> ShowS
UpdateInputDeviceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateInputDeviceResponse] -> ShowS
$cshowList :: [UpdateInputDeviceResponse] -> ShowS
show :: UpdateInputDeviceResponse -> String
$cshow :: UpdateInputDeviceResponse -> String
showsPrec :: Int -> UpdateInputDeviceResponse -> ShowS
$cshowsPrec :: Int -> UpdateInputDeviceResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateInputDeviceResponse x -> UpdateInputDeviceResponse
forall x.
UpdateInputDeviceResponse -> Rep UpdateInputDeviceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateInputDeviceResponse x -> UpdateInputDeviceResponse
$cfrom :: forall x.
UpdateInputDeviceResponse -> Rep UpdateInputDeviceResponse x
Prelude.Generic)
newUpdateInputDeviceResponse ::
Prelude.Int ->
UpdateInputDeviceResponse
newUpdateInputDeviceResponse :: Int -> UpdateInputDeviceResponse
newUpdateInputDeviceResponse Int
pHttpStatus_ =
UpdateInputDeviceResponse'
{ $sel:arn:UpdateInputDeviceResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
$sel:connectionState:UpdateInputDeviceResponse' :: Maybe InputDeviceConnectionState
connectionState = forall a. Maybe a
Prelude.Nothing,
$sel:deviceSettingsSyncState:UpdateInputDeviceResponse' :: Maybe DeviceSettingsSyncState
deviceSettingsSyncState = forall a. Maybe a
Prelude.Nothing,
$sel:deviceUpdateStatus:UpdateInputDeviceResponse' :: Maybe DeviceUpdateStatus
deviceUpdateStatus = forall a. Maybe a
Prelude.Nothing,
$sel:hdDeviceSettings:UpdateInputDeviceResponse' :: Maybe InputDeviceHdSettings
hdDeviceSettings = forall a. Maybe a
Prelude.Nothing,
$sel:id:UpdateInputDeviceResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
$sel:macAddress:UpdateInputDeviceResponse' :: Maybe Text
macAddress = forall a. Maybe a
Prelude.Nothing,
$sel:name:UpdateInputDeviceResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
$sel:networkSettings:UpdateInputDeviceResponse' :: Maybe InputDeviceNetworkSettings
networkSettings = forall a. Maybe a
Prelude.Nothing,
$sel:serialNumber:UpdateInputDeviceResponse' :: Maybe Text
serialNumber = forall a. Maybe a
Prelude.Nothing,
$sel:type':UpdateInputDeviceResponse' :: Maybe InputDeviceType
type' = forall a. Maybe a
Prelude.Nothing,
$sel:uhdDeviceSettings:UpdateInputDeviceResponse' :: Maybe InputDeviceUhdSettings
uhdDeviceSettings = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:UpdateInputDeviceResponse' :: Int
httpStatus = Int
pHttpStatus_
}
updateInputDeviceResponse_arn :: Lens.Lens' UpdateInputDeviceResponse (Prelude.Maybe Prelude.Text)
updateInputDeviceResponse_arn :: Lens' UpdateInputDeviceResponse (Maybe Text)
updateInputDeviceResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInputDeviceResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: UpdateInputDeviceResponse
s@UpdateInputDeviceResponse' {} Maybe Text
a -> UpdateInputDeviceResponse
s {$sel:arn:UpdateInputDeviceResponse' :: Maybe Text
arn = Maybe Text
a} :: UpdateInputDeviceResponse)
updateInputDeviceResponse_connectionState :: Lens.Lens' UpdateInputDeviceResponse (Prelude.Maybe InputDeviceConnectionState)
updateInputDeviceResponse_connectionState :: Lens' UpdateInputDeviceResponse (Maybe InputDeviceConnectionState)
updateInputDeviceResponse_connectionState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInputDeviceResponse' {Maybe InputDeviceConnectionState
connectionState :: Maybe InputDeviceConnectionState
$sel:connectionState:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe InputDeviceConnectionState
connectionState} -> Maybe InputDeviceConnectionState
connectionState) (\s :: UpdateInputDeviceResponse
s@UpdateInputDeviceResponse' {} Maybe InputDeviceConnectionState
a -> UpdateInputDeviceResponse
s {$sel:connectionState:UpdateInputDeviceResponse' :: Maybe InputDeviceConnectionState
connectionState = Maybe InputDeviceConnectionState
a} :: UpdateInputDeviceResponse)
updateInputDeviceResponse_deviceSettingsSyncState :: Lens.Lens' UpdateInputDeviceResponse (Prelude.Maybe DeviceSettingsSyncState)
updateInputDeviceResponse_deviceSettingsSyncState :: Lens' UpdateInputDeviceResponse (Maybe DeviceSettingsSyncState)
updateInputDeviceResponse_deviceSettingsSyncState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInputDeviceResponse' {Maybe DeviceSettingsSyncState
deviceSettingsSyncState :: Maybe DeviceSettingsSyncState
$sel:deviceSettingsSyncState:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe DeviceSettingsSyncState
deviceSettingsSyncState} -> Maybe DeviceSettingsSyncState
deviceSettingsSyncState) (\s :: UpdateInputDeviceResponse
s@UpdateInputDeviceResponse' {} Maybe DeviceSettingsSyncState
a -> UpdateInputDeviceResponse
s {$sel:deviceSettingsSyncState:UpdateInputDeviceResponse' :: Maybe DeviceSettingsSyncState
deviceSettingsSyncState = Maybe DeviceSettingsSyncState
a} :: UpdateInputDeviceResponse)
updateInputDeviceResponse_deviceUpdateStatus :: Lens.Lens' UpdateInputDeviceResponse (Prelude.Maybe DeviceUpdateStatus)
updateInputDeviceResponse_deviceUpdateStatus :: Lens' UpdateInputDeviceResponse (Maybe DeviceUpdateStatus)
updateInputDeviceResponse_deviceUpdateStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInputDeviceResponse' {Maybe DeviceUpdateStatus
deviceUpdateStatus :: Maybe DeviceUpdateStatus
$sel:deviceUpdateStatus:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe DeviceUpdateStatus
deviceUpdateStatus} -> Maybe DeviceUpdateStatus
deviceUpdateStatus) (\s :: UpdateInputDeviceResponse
s@UpdateInputDeviceResponse' {} Maybe DeviceUpdateStatus
a -> UpdateInputDeviceResponse
s {$sel:deviceUpdateStatus:UpdateInputDeviceResponse' :: Maybe DeviceUpdateStatus
deviceUpdateStatus = Maybe DeviceUpdateStatus
a} :: UpdateInputDeviceResponse)
updateInputDeviceResponse_hdDeviceSettings :: Lens.Lens' UpdateInputDeviceResponse (Prelude.Maybe InputDeviceHdSettings)
updateInputDeviceResponse_hdDeviceSettings :: Lens' UpdateInputDeviceResponse (Maybe InputDeviceHdSettings)
updateInputDeviceResponse_hdDeviceSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInputDeviceResponse' {Maybe InputDeviceHdSettings
hdDeviceSettings :: Maybe InputDeviceHdSettings
$sel:hdDeviceSettings:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe InputDeviceHdSettings
hdDeviceSettings} -> Maybe InputDeviceHdSettings
hdDeviceSettings) (\s :: UpdateInputDeviceResponse
s@UpdateInputDeviceResponse' {} Maybe InputDeviceHdSettings
a -> UpdateInputDeviceResponse
s {$sel:hdDeviceSettings:UpdateInputDeviceResponse' :: Maybe InputDeviceHdSettings
hdDeviceSettings = Maybe InputDeviceHdSettings
a} :: UpdateInputDeviceResponse)
updateInputDeviceResponse_id :: Lens.Lens' UpdateInputDeviceResponse (Prelude.Maybe Prelude.Text)
updateInputDeviceResponse_id :: Lens' UpdateInputDeviceResponse (Maybe Text)
updateInputDeviceResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInputDeviceResponse' {Maybe Text
id :: Maybe Text
$sel:id:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: UpdateInputDeviceResponse
s@UpdateInputDeviceResponse' {} Maybe Text
a -> UpdateInputDeviceResponse
s {$sel:id:UpdateInputDeviceResponse' :: Maybe Text
id = Maybe Text
a} :: UpdateInputDeviceResponse)
updateInputDeviceResponse_macAddress :: Lens.Lens' UpdateInputDeviceResponse (Prelude.Maybe Prelude.Text)
updateInputDeviceResponse_macAddress :: Lens' UpdateInputDeviceResponse (Maybe Text)
updateInputDeviceResponse_macAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInputDeviceResponse' {Maybe Text
macAddress :: Maybe Text
$sel:macAddress:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe Text
macAddress} -> Maybe Text
macAddress) (\s :: UpdateInputDeviceResponse
s@UpdateInputDeviceResponse' {} Maybe Text
a -> UpdateInputDeviceResponse
s {$sel:macAddress:UpdateInputDeviceResponse' :: Maybe Text
macAddress = Maybe Text
a} :: UpdateInputDeviceResponse)
updateInputDeviceResponse_name :: Lens.Lens' UpdateInputDeviceResponse (Prelude.Maybe Prelude.Text)
updateInputDeviceResponse_name :: Lens' UpdateInputDeviceResponse (Maybe Text)
updateInputDeviceResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInputDeviceResponse' {Maybe Text
name :: Maybe Text
$sel:name:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateInputDeviceResponse
s@UpdateInputDeviceResponse' {} Maybe Text
a -> UpdateInputDeviceResponse
s {$sel:name:UpdateInputDeviceResponse' :: Maybe Text
name = Maybe Text
a} :: UpdateInputDeviceResponse)
updateInputDeviceResponse_networkSettings :: Lens.Lens' UpdateInputDeviceResponse (Prelude.Maybe InputDeviceNetworkSettings)
updateInputDeviceResponse_networkSettings :: Lens' UpdateInputDeviceResponse (Maybe InputDeviceNetworkSettings)
updateInputDeviceResponse_networkSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInputDeviceResponse' {Maybe InputDeviceNetworkSettings
networkSettings :: Maybe InputDeviceNetworkSettings
$sel:networkSettings:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe InputDeviceNetworkSettings
networkSettings} -> Maybe InputDeviceNetworkSettings
networkSettings) (\s :: UpdateInputDeviceResponse
s@UpdateInputDeviceResponse' {} Maybe InputDeviceNetworkSettings
a -> UpdateInputDeviceResponse
s {$sel:networkSettings:UpdateInputDeviceResponse' :: Maybe InputDeviceNetworkSettings
networkSettings = Maybe InputDeviceNetworkSettings
a} :: UpdateInputDeviceResponse)
updateInputDeviceResponse_serialNumber :: Lens.Lens' UpdateInputDeviceResponse (Prelude.Maybe Prelude.Text)
updateInputDeviceResponse_serialNumber :: Lens' UpdateInputDeviceResponse (Maybe Text)
updateInputDeviceResponse_serialNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInputDeviceResponse' {Maybe Text
serialNumber :: Maybe Text
$sel:serialNumber:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe Text
serialNumber} -> Maybe Text
serialNumber) (\s :: UpdateInputDeviceResponse
s@UpdateInputDeviceResponse' {} Maybe Text
a -> UpdateInputDeviceResponse
s {$sel:serialNumber:UpdateInputDeviceResponse' :: Maybe Text
serialNumber = Maybe Text
a} :: UpdateInputDeviceResponse)
updateInputDeviceResponse_type :: Lens.Lens' UpdateInputDeviceResponse (Prelude.Maybe InputDeviceType)
updateInputDeviceResponse_type :: Lens' UpdateInputDeviceResponse (Maybe InputDeviceType)
updateInputDeviceResponse_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInputDeviceResponse' {Maybe InputDeviceType
type' :: Maybe InputDeviceType
$sel:type':UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe InputDeviceType
type'} -> Maybe InputDeviceType
type') (\s :: UpdateInputDeviceResponse
s@UpdateInputDeviceResponse' {} Maybe InputDeviceType
a -> UpdateInputDeviceResponse
s {$sel:type':UpdateInputDeviceResponse' :: Maybe InputDeviceType
type' = Maybe InputDeviceType
a} :: UpdateInputDeviceResponse)
updateInputDeviceResponse_uhdDeviceSettings :: Lens.Lens' UpdateInputDeviceResponse (Prelude.Maybe InputDeviceUhdSettings)
updateInputDeviceResponse_uhdDeviceSettings :: Lens' UpdateInputDeviceResponse (Maybe InputDeviceUhdSettings)
updateInputDeviceResponse_uhdDeviceSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInputDeviceResponse' {Maybe InputDeviceUhdSettings
uhdDeviceSettings :: Maybe InputDeviceUhdSettings
$sel:uhdDeviceSettings:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe InputDeviceUhdSettings
uhdDeviceSettings} -> Maybe InputDeviceUhdSettings
uhdDeviceSettings) (\s :: UpdateInputDeviceResponse
s@UpdateInputDeviceResponse' {} Maybe InputDeviceUhdSettings
a -> UpdateInputDeviceResponse
s {$sel:uhdDeviceSettings:UpdateInputDeviceResponse' :: Maybe InputDeviceUhdSettings
uhdDeviceSettings = Maybe InputDeviceUhdSettings
a} :: UpdateInputDeviceResponse)
updateInputDeviceResponse_httpStatus :: Lens.Lens' UpdateInputDeviceResponse Prelude.Int
updateInputDeviceResponse_httpStatus :: Lens' UpdateInputDeviceResponse Int
updateInputDeviceResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInputDeviceResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateInputDeviceResponse
s@UpdateInputDeviceResponse' {} Int
a -> UpdateInputDeviceResponse
s {$sel:httpStatus:UpdateInputDeviceResponse' :: Int
httpStatus = Int
a} :: UpdateInputDeviceResponse)
instance Prelude.NFData UpdateInputDeviceResponse where
rnf :: UpdateInputDeviceResponse -> ()
rnf UpdateInputDeviceResponse' {Int
Maybe Text
Maybe DeviceSettingsSyncState
Maybe DeviceUpdateStatus
Maybe InputDeviceConnectionState
Maybe InputDeviceNetworkSettings
Maybe InputDeviceHdSettings
Maybe InputDeviceType
Maybe InputDeviceUhdSettings
httpStatus :: Int
uhdDeviceSettings :: Maybe InputDeviceUhdSettings
type' :: Maybe InputDeviceType
serialNumber :: Maybe Text
networkSettings :: Maybe InputDeviceNetworkSettings
name :: Maybe Text
macAddress :: Maybe Text
id :: Maybe Text
hdDeviceSettings :: Maybe InputDeviceHdSettings
deviceUpdateStatus :: Maybe DeviceUpdateStatus
deviceSettingsSyncState :: Maybe DeviceSettingsSyncState
connectionState :: Maybe InputDeviceConnectionState
arn :: Maybe Text
$sel:httpStatus:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Int
$sel:uhdDeviceSettings:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe InputDeviceUhdSettings
$sel:type':UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe InputDeviceType
$sel:serialNumber:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe Text
$sel:networkSettings:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe InputDeviceNetworkSettings
$sel:name:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe Text
$sel:macAddress:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe Text
$sel:id:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe Text
$sel:hdDeviceSettings:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe InputDeviceHdSettings
$sel:deviceUpdateStatus:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe DeviceUpdateStatus
$sel:deviceSettingsSyncState:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe DeviceSettingsSyncState
$sel:connectionState:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe InputDeviceConnectionState
$sel:arn:UpdateInputDeviceResponse' :: UpdateInputDeviceResponse -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InputDeviceConnectionState
connectionState
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeviceSettingsSyncState
deviceSettingsSyncState
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeviceUpdateStatus
deviceUpdateStatus
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InputDeviceHdSettings
hdDeviceSettings
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
macAddress
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InputDeviceNetworkSettings
networkSettings
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
serialNumber
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InputDeviceType
type'
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InputDeviceUhdSettings
uhdDeviceSettings
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus